InitDiversions Subroutine

public subroutine InitDiversions(fileIni)

Initialize diversions

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fileIni

diversion configuration file


Variables

Type Visibility Attributes Name Initial
character(len=100), public, POINTER :: args(:)
type(Diversion), public, POINTER :: currentDiversion
integer(kind=short), public, ALLOCATABLE :: doy(:)
integer(kind=short), public :: i
type(IniList), public :: iniDB
type(Table), public :: initialQ
integer(kind=short), public :: j
integer(kind=short), public :: k
integer(kind=short), public :: nArgs
character(len=300), public :: string

Source Code

SUBROUTINE InitDiversions  &
!
(fileIni)

IMPLICIT NONE

!arguments with intent in:
CHARACTER (LEN=*), INTENT(IN)     :: fileIni !!diversion configuration file


!local declarations
TYPE (IniList)   :: iniDB
TYPE (Diversion), POINTER :: currentDiversion !points to current diversion
CHARACTER (LEN = 300)     :: string
INTEGER (KIND = short)    :: nArgs 
INTEGER (KIND = short)    :: k, i, j
CHARACTER (len=100), POINTER   :: args(:)
INTEGER(KIND = short), ALLOCATABLE :: doy (:)
TYPE (Table) :: initialQ ! for discharge initialization from previous simulation



!-------------------------------end of declaration-----------------------------

CALL Catch ('info', 'Diversions', 'Initializing diversion channels ')

!--------------------------------------------
!  open and read configuration file
!--------------------------------------------

CALL IniOpen (fileIni, iniDB)

!--------------------------------------------
!  allocate and populate diversion channels 
!--------------------------------------------

nDiversions =  IniReadInt ('ndiversions', iniDB)

!prepare list of reservoirs
 NULLIFY (diversionChannels)
 DO k = 1, nDiversions
   IF (.NOT. ASSOCIATED (diversionChannels) ) THEN
     ALLOCATE (diversionChannels)
     currentDiversion => diversionChannels
   ELSE
     ALLOCATE (currentDiversion % next)
     currentDiversion => currentDiversion % next
   END IF
   
   !id
   currentDiversion % id = &
       IniReadInt ('id', iniDB, section = ToString(k))
   
   !name
   currentDiversion % name = &
       IniReadString ('name', iniDB, section = ToString(k))
   
   !coordinate
   currentDiversion % xyz % easting = &
       IniReadReal ('easting', iniDB, section = ToString(k))
   currentDiversion % xyz % northing = &
       IniReadReal ('northing', iniDB, section = ToString(k))
   currentDiversion % xyz % system = &
       DecodeEpsg (IniReadInt ('epsg', iniDB))
   
   !read x and y coordinate where outflow from diversion is discharged
   currentDiversion % xout = &
       IniReadReal ('xout', iniDB, section = ToString(k))
   currentDiversion % yout = &
       IniReadReal ('yout', iniDB, section = ToString(k))
       
   !local coordinate
   CALL GetIJ ( X = currentDiversion % xyz % easting, &
                Y = currentDiversion % xyz % northing, &
                grid = mask, i = currentDiversion % r, &
                j = currentDiversion % c )
   
   CALL GetIJ ( X = currentDiversion % xout, &
                Y = currentDiversion % yout, &
                grid = mask, i = currentDiversion % rout, &
                j = currentDiversion % cout )
   
   !read weir data
   CALL ReadWeir (iniDB, k, currentDiversion )
   
   !channel lenght
   currentDiversion % channelLenght = &
           IniReadReal ('channel-lenght', iniDB, section = ToString(k) )
   !channel slope
   currentDiversion % channelSlope = &
           IniReadReal ('channel-slope', iniDB, section = ToString(k) )
   !channel roughness coefficient
   currentDiversion % channelManning = &
           IniReadReal ('channel-manning', iniDB, section = ToString(k) )
   !channel section bottom width
   currentDiversion % channelWidth = &
           IniReadReal ('section-bottom-width', iniDB, section = ToString(k) )
   !channel section bank slope
   currentDiversion % channelBankSlope = &
           IniReadReal ('section-bank-slope', iniDB, section = ToString(k) )
   
    !environmental flow
    IF ( KeyIsPresent ('e-flow', iniDB, section = ToString(k) ) ) THEN
       string = IniReadString ('e-flow', iniDB, section = ToString(k))
       currentDiversion % eFlow = SetDailyArray (string)
    ELSE !e-flow = 0.
      currentDiversion % eFlow = 0.
    END IF
          
   
 END DO

!--------------------------------------------
!  initialize discharge value 
!--------------------------------------------
 
IF ( KeyIsPresent ('path-hotstart', iniDB ) ) THEN
    !read file to initialize discharge
    string = IniReadString ('path-hotstart', iniDB )
    write(*,*) trim(string)
    CALL TableNew ( string, initialQ )
    write(*,*) 'fine TableNew'
    currentDiversion => diversionChannels
    write(*,*) nDiversions
    DO i = 1, nDiversions
        string = TRIM ( ToString ( currentDiversion % id ) )
        write(*,*) trim(string)
        CALL TableGetValue ( string, initialQ, 'id', 'Qin', &
                             currentDiversion % PinChannel  )
        CALL TableGetValue ( string, initialQ, 'id', 'Qout', &
                             currentDiversion % PoutChannel  )
        write(*,*) currentDiversion % PinChannel , currentDiversion % PoutChannel
        currentDiversion => currentDiversion % next
    END DO
END IF

!--------------------------------------------
!  close configuration file
!--------------------------------------------

CALL IniClose (iniDb)


RETURN
END SUBROUTINE InitDiversions